home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / DDJMAG / DDJ9207.ZIP / GRPHPROG.ASC < prev    next >
Text File  |  1992-06-15  |  15KB  |  351 lines

  1. _GRAPHICS PROGRAMMING COLUMN_
  2. by Michael Abrash
  3.  
  4. [LISTING ONE]
  5.  
  6. ; Fixed point multiply and divide routines. Tested with TASM 3.0.
  7. USE386      equ 1   ;1 for 386-specific opcodes, 0 for 8088 opcodes
  8. MUL_ROUNDING_ON equ 1   ;1 for rounding on multiplies, 0 for no 
  9.                                 ; rounding. Not rounding is faster, rounding is
  10.                                 ; more accurate and generally a good idea
  11. DIV_ROUNDING_ON equ 0   ;1 for rounding on divides, 0 for no rounding. 
  12.                                 ; Not rounding is faster, rounding is more 
  13.                                 ; accurate, but because division is only 
  14.                                 ; performed to project to the screen, rounding 
  15.                                 ; quotients generally isn't necessary
  16. ALIGNMENT   equ 2
  17.     .model small
  18.     .386
  19.     .code
  20. ;=====================================================================
  21. ; Multiplies two fixed-point values together. C near-callable as:
  22. ;   Fixedpoint FixedMul(Fixedpoint M1, Fixedpoint M2);
  23. FMparms struc
  24.     dw  2 dup(?)    ;return address & pushed BP
  25. M1  dd  ?
  26. M2  dd  ?
  27. FMparms ends
  28.     align   ALIGNMENT
  29.     public  _FixedMul
  30. _FixedMul       proc    near
  31.         push    bp
  32.         mov     bp,sp
  33. if USE386
  34.         mov     eax,[bp+M1]
  35.         imul    dword ptr [bp+M2] ;multiply
  36. if MUL_ROUNDING_ON
  37.         add     eax,8000h       ;round by adding 2^(-17)
  38.         adc     edx,0           ;whole part of result is in DX
  39. endif ;MUL_ROUNDING_ON
  40.         shr     eax,16          ;put the fractional part in AX
  41. else    ;!USE386
  42.                 ;do four partial products and add them 
  43.                 ; together, accumulating the result in CX:BX
  44.     push    si      ;preserve C register variables
  45.     push    di
  46.                ;figure out signs, so we can use unsigned multiplies
  47.     sub cx,cx       ;assume both operands positive
  48.     mov ax,word ptr [bp+M1+2]
  49.     mov si,word ptr [bp+M1]
  50.     and ax,ax       ;first operand negative?
  51.     jns CheckSecondOperand ;no
  52.     neg ax      ;yes, so negate first operand
  53.     neg si
  54.     sbb ax,0
  55.     inc cx      ;mark that first operand is negative
  56. CheckSecondOperand:
  57.     mov bx,word ptr [bp+M2+2]
  58.     mov di,word ptr [bp+M2]
  59.     and bx,bx       ;second operand negative?
  60.     jns SaveSignStatus  ;no
  61.     neg bx      ;yes, so negate second operand
  62.     neg di
  63.     sbb bx,0
  64.     xor cx,1        ;mark that second operand is negative
  65. SaveSignStatus:
  66.     push    cx      ;remember sign of result; 1 if result
  67.                 ; negative, 0 if result nonnegative
  68.     push    ax      ;remember high word of M1
  69.     mul bx      ;high word M1 times high word M2
  70.     mov cx,ax       ;accumulate result in CX:BX (BX not used until
  71.                                 ; next operation) assume no overflow into DX
  72.     mov ax,si       ;low word M1 times high word M2
  73.     mul bx
  74.     mov bx,ax
  75.     add cx,dx       ;accumulate result in CX:BX
  76.     pop ax      ;retrieve high word of M1
  77.     mul di      ;high word M1 times low word M2
  78.     add bx,ax
  79.     adc cx,dx       ;accumulate result in CX:BX
  80.     mov ax,si       ;low word M1 times low word M2
  81.     mul di
  82. if MUL_ROUNDING_ON
  83.         add     ax,8000h    ;round by adding 2^(-17)
  84.     adc bx,dx
  85. else ;!MUL_ROUNDING_ON
  86.     add bx,dx       ;don't round
  87. endif ;MUL_ROUNDING_ON
  88.     adc cx,0        ;accumulate result in CX:BX
  89.     mov dx,cx
  90.     mov ax,bx
  91.     pop cx
  92.     and cx,cx       ;is the result negative?
  93.     jz  FixedMulDone    ;no, we're all set
  94.     neg dx      ;yes, so negate DX:AX
  95.     neg ax
  96.     sbb dx,0
  97. FixedMulDone:
  98.     pop di      ;restore C register variables
  99.     pop si
  100. endif   ;USE386
  101.         pop     bp
  102.         ret
  103. _FixedMul       endp
  104. ;=====================================================================
  105. ; Divides one fixed-point value by another. C near-callable as:
  106. ;   Fixedpoint FixedDiv(Fixedpoint Dividend, Fixedpoint Divisor);
  107. FDparms struc
  108.     dw  2 dup(?)    ;return address & pushed BP
  109. Dividend dd ?
  110. Divisor  dd ?
  111. FDparms ends
  112.     align   ALIGNMENT
  113.     public  _FixedDiv
  114. _FixedDiv       proc    near
  115.         push    bp
  116.         mov     bp,sp
  117. if USE386
  118. if DIV_ROUNDING_ON
  119.         sub     cx,cx           ;assume positive result
  120.         mov     eax,[bp+Dividend]
  121.         and     eax,eax         ;positive dividend?
  122.         jns     FDP1            ;yes
  123.         inc     cx              ;mark it's a negative dividend
  124.         neg     eax             ;make the dividend positive
  125. FDP1:   sub     edx,edx         ;make it a 64-bit dividend, then shift
  126.                                 ; left 16 bits so that result will be in EAX
  127.         rol     eax,16          ;put fractional part of dividend in 
  128.                                 ; high word of EAX
  129.         mov     dx,ax           ;put whole part of dividend in DX
  130.         sub     ax,ax           ;clear low word of EAX
  131.         mov     ebx,dword ptr [bp+Divisor]
  132.         and     ebx,ebx         ;positive divisor?
  133.         jns     FDP2            ;yes
  134.         dec     cx              ;mark it's a negative divisor
  135.         neg     ebx             ;make divisor positive
  136. FDP2:   div     ebx             ;divide
  137.         shr     ebx,1           ;divisor/2, minus 1 if the divisor is
  138.         adc     ebx,0           ; even
  139.         dec     ebx
  140.         cmp     ebx,edx         ;set Carry if the remainder is at least
  141.         adc     eax,0           ; half as large as the divisor, then
  142.                                 ; use that to round up if necessary
  143.         and     cx,cx           ;should the result be made negative?
  144.         jz      FDP3            ;no
  145.         neg     eax             ;yes, negate it
  146. FDP3:
  147. else ;!DIV_ROUNDING_ON
  148.     mov edx,[bp+Dividend]
  149.     sub eax,eax
  150.     shrd    eax,edx,16  ;position so that result ends up
  151.     sar edx,16      ; in EAX
  152.     idiv    dword ptr [bp+Divisor]
  153. endif ;DIV_ROUNDING_ON
  154.     shld    edx,eax,16  ;whole part of result in DX;
  155.                     ; fractional part is already in AX
  156. else ;!USE386
  157. ;NOTE!!! Non-386 division uses a 32-bit dividend but only the upper 16 bits
  158. ; of the divisor; in other words, only the integer part of the divisor is
  159. ; used. This is done so that the division can be accomplished with two fast
  160. ; hardware divides instead of a slow software implementation, and is (in my
  161. ; opinion) acceptable because division is only used to project points to the
  162. ; screen (normally, the divisor is a Z coordinate), so there's no cumulative
  163. ; error, although there will be some error in pixel placement (the magnitude
  164. ; of the error is less the farther away from the Z=0 plane objects are). This
  165. ; is *not* a general-purpose divide, though; if the divisor is less than 1,
  166. ; for instance, a divide-by-zero error will result! For this reason, non-386
  167. ; projection can't be performed for points closer to the viewpoint than Z=1.
  168.                 ;figure out signs, so we can use
  169.                 ; unsigned divisions
  170.     sub cx,cx       ;assume both operands positive
  171.     mov ax,word ptr [bp+Dividend+2]
  172.     and ax,ax       ;first operand negative?
  173.     jns CheckSecondOperandD ;no
  174.     neg ax      ;yes, so negate first operand
  175.     neg word ptr [bp+Dividend]
  176.     sbb ax,0
  177.     inc cx      ;mark that first operand is negative
  178. CheckSecondOperandD:
  179.     mov bx,word ptr [bp+Divisor+2]
  180.     and bx,bx       ;second operand negative?
  181.     jns SaveSignStatusD ;no
  182.     neg bx      ;yes, so negate second operand
  183.     neg word ptr [bp+Divisor]
  184.     sbb bx,0
  185.     xor cx,1        ;mark that second operand is negative
  186. SaveSignStatusD:
  187.     push    cx      ;remember sign of result; 1 if result
  188.                 ; negative, 0 if result nonnegative
  189.     sub dx,dx       ;put Dividend+2 (integer part) in DX:AX
  190.     div bx      ;first half of 32/16 division, integer part
  191.                 ; divided by integer part
  192.     mov cx,ax       ;set aside integer part of result
  193.     mov ax,word ptr [bp+Dividend] ;concatenate the fractional part of
  194.                 ; the dividend to the remainder (fractional
  195.                 ; part) of the result from dividing the
  196.                 ; integer part of the dividend
  197.     div bx      ;second half of 32/16 division
  198. if DIV_ROUNDING_ON EQ 0
  199.         shr     bx,1            ;divisor/2, minus 1 if the divisor is
  200.         adc     bx,0            ; even
  201.         dec     bx
  202.         cmp     bx,dx           ;set Carry if the remainder is at least
  203.         adc     ax,0            ; half as large as the divisor, then
  204.     adc cx,0            ; use that to round up if necessary
  205. endif ;DIV_ROUNDING_ON
  206.     mov dx,cx       ;absolute value of result in DX:AX
  207.     pop cx
  208.     and cx,cx       ;is the result negative?
  209.     jz  FixedDivDone    ;no, we're all set
  210.     neg dx      ;yes, so negate DX:AX
  211.     neg ax
  212.     sbb dx,0
  213. FixedDivDone:
  214. endif ;USE386
  215.         pop     bp
  216.         ret
  217. _FixedDiv       endp
  218.     end
  219.  
  220.  
  221. [LISTING TWO]
  222.  
  223. /* Draws all visible faces in the specified polygon-based object. The object 
  224.    must have previously been transformed and projected, so that all vertex 
  225.    arrays are filled in. Ambient and diffuse shading are supported. */
  226. #include "polygon.h"
  227.  
  228. void DrawPObject(PObject * ObjectToXform)
  229. {
  230.    int i, j, NumFaces = ObjectToXform->NumFaces, NumVertices;
  231.    int * VertNumsPtr, Spot;
  232.    Face * FacePtr = ObjectToXform->FaceList;
  233.    Point * ScreenPoints = ObjectToXform->ScreenVertexList;
  234.    PointListHeader Polygon;
  235.    Fixedpoint Diffusion;
  236.    ModelColor ColorTemp;
  237.    ModelIntensity IntensityTemp;
  238.    Point3 UnitNormal, *NormalStartpoint, *NormalEndpoint;
  239.    long v1, v2, w1, w2;
  240.    Point Vertices[MAX_POLY_LENGTH];
  241.  
  242.    /* Draw each visible face (polygon) of the object in turn */
  243.    for (i=0; i<NumFaces; i++, FacePtr++) {
  244.       /* Remember where we can find the start and end of the polygon's
  245.          unit normal in view space, and skip over the unit normal endpoint
  246.          entry. The end and start points of the unit normal to the polygon
  247.          must be the first and second entries in the polgyon's vertex list.
  248.          Note that the second point is also an active polygon vertex */
  249.       VertNumsPtr = FacePtr->VertNums;
  250.       NormalEndpoint = &ObjectToXform->XformedVertexList[*VertNumsPtr++];
  251.       NormalStartpoint = &ObjectToXform->XformedVertexList[*VertNumsPtr];
  252.       /* Copy over the face's vertices from the vertex list */
  253.       NumVertices = FacePtr->NumVerts;
  254.       for (j=0; j<NumVertices; j++)
  255.          Vertices[j] = ScreenPoints[*VertNumsPtr++];
  256.       /* Draw only if outside face showing (if the normal to the polygon
  257.          in screen coordinates points toward the viewer; that is, has a
  258.          positive Z component) */
  259.       v1 = Vertices[1].X - Vertices[0].X;
  260.       w1 = Vertices[NumVertices-1].X - Vertices[0].X;
  261.       v2 = Vertices[1].Y - Vertices[0].Y;
  262.       w2 = Vertices[NumVertices-1].Y - Vertices[0].Y;
  263.       if ((v1*w2 - v2*w1) > 0) {
  264.          /* It is facing the screen, so draw */
  265.          /* Appropriately adjust the extent of the rectangle used to
  266.             erase this object later */
  267.          for (j=0; j<NumVertices; j++) {
  268.             if (Vertices[j].X >
  269.                   ObjectToXform->EraseRect[NonDisplayedPage].Right)
  270.                if (Vertices[j].X < SCREEN_WIDTH)
  271.                   ObjectToXform->EraseRect[NonDisplayedPage].Right =
  272.                         Vertices[j].X;
  273.                else ObjectToXform->EraseRect[NonDisplayedPage].Right =
  274.                      SCREEN_WIDTH;
  275.             if (Vertices[j].Y >
  276.                   ObjectToXform->EraseRect[NonDisplayedPage].Bottom)
  277.                if (Vertices[j].Y < SCREEN_HEIGHT)
  278.                   ObjectToXform->EraseRect[NonDisplayedPage].Bottom =
  279.                         Vertices[j].Y;
  280.                else ObjectToXform->EraseRect[NonDisplayedPage].Bottom=
  281.                      SCREEN_HEIGHT;
  282.             if (Vertices[j].X <
  283.                   ObjectToXform->EraseRect[NonDisplayedPage].Left)
  284.                if (Vertices[j].X > 0)
  285.                   ObjectToXform->EraseRect[NonDisplayedPage].Left =
  286.                         Vertices[j].X;
  287.                else ObjectToXform->EraseRect[NonDisplayedPage].Left=0;
  288.             if (Vertices[j].Y <
  289.                   ObjectToXform->EraseRect[NonDisplayedPage].Top)
  290.                if (Vertices[j].Y > 0)
  291.                   ObjectToXform->EraseRect[NonDisplayedPage].Top =
  292.                         Vertices[j].Y;
  293.                else ObjectToXform->EraseRect[NonDisplayedPage].Top=0;
  294.          }
  295.          /* See if there's any shading */
  296.             if (FacePtr->ShadingType == 0) {
  297.             /* No shading in effect, so just draw */
  298.             DRAW_POLYGON(Vertices, NumVertices, FacePtr->ColorIndex, 0, 0);
  299.          } else {
  300.             /* Handle shading */
  301.             /* Do ambient shading, if enabled */
  302.             if (AmbientOn && (FacePtr->ShadingType & AMBIENT_SHADING)) {
  303.                /* Use the ambient shading component */
  304.                IntensityTemp = AmbientIntensity;
  305.             } else {
  306.                SET_INTENSITY(IntensityTemp, 0, 0, 0);
  307.             }
  308.             /* Do diffuse shading, if enabled */
  309.             if (FacePtr->ShadingType & DIFFUSE_SHADING) {
  310.                /* Calculate the unit normal for this polygon, for use in dot
  311.                   products */
  312.                UnitNormal.X = NormalEndpoint->X - NormalStartpoint->X;
  313.                UnitNormal.Y = NormalEndpoint->Y - NormalStartpoint->Y;
  314.                UnitNormal.Z = NormalEndpoint->Z - NormalStartpoint->Z;
  315.                /* Calculate the diffuse shading component for each active
  316.                   spotlight */
  317.                for (Spot=0; Spot<MAX_SPOTS; Spot++) {
  318.                   if (SpotOn[Spot] != 0) {
  319.                      /* Spot is on, so sum, for each color component, the
  320.                         intensity, accounting for the angle of the light rays
  321.                         relative to the orientation of the polygon */
  322.                      /* Calculate cosine of angle between the light and the
  323.                         polygon normal; skip if spot is shining from behind
  324.                         the polygon */
  325.                      if ((Diffusion = DOT_PRODUCT(SpotDirectionView[Spot],
  326.                            UnitNormal)) > 0) {
  327.                         IntensityTemp.Red +=
  328.                               FixedMul(SpotIntensity[Spot].Red, Diffusion);
  329.                         IntensityTemp.Green +=
  330.                               FixedMul(SpotIntensity[Spot].Green, Diffusion);
  331.                         IntensityTemp.Blue +=
  332.                               FixedMul(SpotIntensity[Spot].Blue, Diffusion);
  333.                      }
  334.                   }
  335.                }
  336.             }
  337.             /* Convert the drawing color to the desired fraction of the
  338.                brightest possible color */
  339.             IntensityAdjustColor(&ColorTemp, &FacePtr->FullColor,
  340.                   &IntensityTemp);
  341.             /* Draw with the cumulative shading, converting from the general
  342.                color representation to the best-match color index */
  343.             DRAW_POLYGON(Vertices, NumVertices,
  344.                   ModelColorToColorIndex(&ColorTemp), 0, 0);
  345.          }
  346.       }
  347.    }
  348. }
  349.  
  350.  
  351.